home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
smaltalk
/
manchest.lha
/
MANCHESTER
/
manchester
/
4.1
/
interactors
/
Interactors-Support.st
< prev
next >
Wrap
Text File
|
1993-07-24
|
4KB
|
129 lines
Object subclass: #IdentityWrapper
instanceVariableNames: 'value '
classVariableNames: ''
poolDictionaries: ''
category: 'Interactors-Support'!
!IdentityWrapper methodsFor: 'acessing'!
value
^value! !
!IdentityWrapper methodsFor: 'private'!
setValue: aValue
value := aValue! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
IdentityWrapper class
instanceVariableNames: ''!
!IdentityWrapper class methodsFor: 'instance creation'!
on: aValue
^super new setValue: aValue! !
TextItemEditor subclass: #TextFieldEditor
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Interactors-Support'!
!TextFieldEditor methodsFor: 'initialize-release'!
initialize
super initialize.
self crBlock: [self view container accepted]! !
!TextFieldEditor methodsFor: 'control defaults'!
isControlActive
^self sensor blueButtonPressed not
and: [view bounds containsPoint: self sensor cursorPoint]! !
!TextFieldEditor methodsFor: 'editing'!
replaceFrom: start to: stop with: aText
"Replace the receiver's text starting at position start, stopping at stop,
by the characters in aText."
| changeInfo startLine affectedLines lineDelta |
self textHasChanged: true.
self text size = 0
ifTrue: [self paragraph replaceFrom: start to: stop with: aText.
view invalidate]
ifFalse: [| lineIndex |
lineIndex := self paragraph lineIndexOfCharacterIndex: start.
changeInfo :=self paragraph replaceFrom: start to: stop with: aText.
startLine := changeInfo at: 1.
affectedLines := changeInfo at: 3.
lineDelta := changeInfo at: 2.
(lineDelta = 0 and:
[affectedLines = 1 and:
[view textStyle alignment = LeftFlush and:
[view startBlock top = (view topAtLineIndex: startLine)]]])
ifTrue: [ | sb rect lineLast gc |
sb := view startBlock.
gc := view graphicsContext.
(gc clippingBounds containsPoint: sb origin)
ifFalse: [^self].
lineLast := (self paragraph lineAt: lineIndex) last.
(self text string at: lineLast) == Character cr
ifTrue: [lineLast := lineLast -1].
rect := Rectangle origin: sb left@sb top
corner: view clippingBox right@sb bottom.
(start < lineLast or: [(stop < start) not or: [aText size = 0]])
ifTrue: [gc paint: view backgroundColor.
gc displayRectangle: rect].
gc paint: view foregroundColor.
self paragraph displayFromCharacter: start to: lineLast startX: rect left
forTranslation: view displayOrigin on: gc]
ifFalse: [view
redisplayAfterReplacementAt: startLine
affectedLines: affectedLines
lineDelta: lineDelta]].! !
ComposedTextView subclass: #TextFieldView
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Interactors-Support'!
!TextFieldView methodsFor: 'initialize-release'!
initialDisplayContents
^'' asComposedText! !
!TextFieldView methodsFor: 'controller access'!
defaultControllerClass
"Answer the default controller class for the receiver."
^TextFieldEditor! !
!TextFieldView methodsFor: 'displaying'!
displayOn: aGC
aGC clippingRectangle: nil.
super displayOn: aGC.
controller trackMouseSelection "cheap trick to cause insertion point to be displayed"!
invalidate
^container render! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
TextFieldView class
instanceVariableNames: ''!
!TextFieldView class methodsFor: 'instance creation'!
on: aStringOrText
^self new editText: aStringOrText asText! !